.TITLE IISRV .IDENT /03.11/ ;+ ; Copyright (c) 1995-1999 by Mentec, Inc., U.S.A. ; All rights reserved ; ; This software is furnished under a license and may only be used ; or copied in accordance with the terms of such license. ; ; ; K. E. Kinnear 11-Nov-77 ; ; Modified by: ; ; J. W. Berzle 08-Sep-83 03.00 ; ; JWB047 -- Add bugcheck facility and error codes ; ; D. T. Carroll November, 1989 03.10 ; ; Tally CPU ticks/per mode during sanity timer update ; ; D. T. Carroll September, 1990 03.20 ; ; Include support in IIOPN to disable auxillary sanity ; timers during offline processing. ; ; D. Carroll 18-Oct-1995 03.21 ; DC404 - Include PSECT statement to allow ICB pool expansion ; ; ; Interprocessor Interrupt Service subroutines ; ; Macro library calls ; .IF DF M$$PRO .MCALL HWDDF$,BGCK$A,ACNDF$ HWDDF$ ; Define hardware registers ACNDF$ ; Define accounting offsets .IIF DF,K$$DAS&I$$CBP, .PSECT EXEC1 ;DC404 ; ; IIST CSR definitions and status bits ; PGTE=0 ; Program generated transmit enables PGCS=1 ; Program generated CSR GO=1 ; Pgcs go bit IE=4 ; Pgcs interrupt enable IP=10 ; Pgcs interrupt pending RDY=4000 ; Pgcs ready to accept command ERR=100000 ; Pgcs error summary bit STTE=2 ; Sanity timer transmit enable STCS=3 ; Sanity timer CSR ENB=1 ; Stcs enable count STP=2 ; Stcs stop count LKE=4 ; Stcs lockup processor if timeout IMSK=4 ; Interrupt mask register - 1=disable PGF=5 ; Program generated interrupt flags STF=6 ; Sanity timer interrupt flags register DCF=7 ; DCLO / Disconnect register EXC=10 ; Exception register MTC=15 ; Maintenance control register B.CPAT = B.RLOD+4 ; Define offset for CPA's info .SBTTL $IISTM, Set IIST enable masks ;+ ; **-$IISTM- Set all Interprocessor Interrupt enable interrupt masks. ; ; This routine will reset the interrupt mask in the IIST for this processor ; and notify all others that their interrupt masks must also be changed. ; when the routine returns, all processors have reset their masks. ; ; Inputs: ; ; $IIMSK=desired interrupt mask for all processors. ; ; Outputs: ; ; R2=mask of processors who didn't reset their masks (if any). ; ; No registers are preserved. ;- $IISTM::CALL $IISLM ; Set the local masks MOV #MP.RSM,R2 ; Set reset masks function CALLR $IISFA ; Send function to all online CPUs ; And wait for acknowledgement .SBTTL $IINIT, Interprocessor Interrupt Initialization ;+ ; **-$IINIT- Interprocessor Interrupt initialization ; **-$IIPWF- Interprocessor Interrupt powerfail service. ; ; This routine will validate the existance of an IIST, and then ; Set the local interrupt masks and the interrupt enable. ; ; Inputs: ; ; None. ; ; Outputs: ; ; None. ; ; No registers are preserved. ;- $IINIT:: ; Reference label $IIPWF::CALL $IISLM ; Set local interrupt masks CALL $IISIE ; Set interrupt enable CALL $IIKRB ; Get current IIST KRB address CALL $SGFIN ; Disable Nxm traps ... MOV (R4),R5 ; get the Primary CSR address BIC #KS.EXT,K.STS(R4) ; not parallel (secondary IIST) MFPS -(SP) ; save current PSW BISB K.PRI(R4),PS ; raise to device priority MOVB 5(R5),R5 ;;; get the IIST self-ID BCS 20$ ;;; if CS, CSR doesn't exist BIC #^C<3>,R5 ;;; isolate the self-ID bits CMPB R5,$PROCN ;;; correct ID word? BNE 20$ ;;; nope, not a secondary IIST BIS #KS.EXT,K.STS(R4) ;;; flag secondary IIST available MOV (R4),R5 ;;; extract the CSR again BIS #100000,4(R5) ;;; reset the secondary IIST 20$: MTPS (SP)+ ;;; restore previous PSW RETURN ; to caller, function complete .SBTTL $IISLM, Set local Interprocessor interrupt masks ;+ ; **-$IISLM- Set local Interprocessor Interrupt masks. ; ; This routine will set the local interprocessor interrupt masks ; To the value in $IIMSK ; ; Inputs: ; ; $IIMSK=desired value of local interrupt mask. ; ; Outputs: ; ; None. ; ; R0, R1, R2, and R3 are preserved. ;- $IISLM::CALL $IIKRB ; Get IIST KRB if online, else return MFPS -(SP) ; Save priority CACHE$ BYPASS ; Make sure we get right one MOV $IIMSK,-(SP) ; Get desired mask setting CACHE$ RESTOR ; Unbypass MOV (SP),-(SP) ; Copy top of stack COM (SP) ; Change state for IIST BIC #177760,(SP) ; Make it processors only BIS #7400,(SP) ; Don't allow boots MOV (R4),R5 ; Get CSR address BISB K.PRI(R4),@#PS ; Increase priority, don't decrease MOV #DCF,(R5) ; Get disconnected CPU flags MOV 2(R5),-(SP) ; Into top of stack SWAB (SP) ; Put disconnect flags in lower byte BIC $CPMSK,(SP) ; Only processors that we care about BIS (SP),2(SP) ; Disallow interrupts from these CPUs MOV (SP)+,K.CRQ(R4) ; Save mask of broken connections MOV #IMSK,(R5) ;;; Select interrupt mask register MOV (SP)+,2(R5) ;;; Load interrupt masks BIC #177760,(SP) ;;; Make it just CPUs MOV (SP),-(SP) ;;; Duplicate stack contents MOV #1,R4 ;;; Initialize odd parity CLC ;;; Set up initial carry bit ROR (SP) ;;; Check low order bit BEQ 20$ ;;; If EQ eq ADC R4 ;;; Accumulate parity bits 10$: ASR (SP) ;;; Get next bit in word BEQ 20$ ;;; End of all bits ADC R4 ;;; Accumulate parity bits BR 10$ ;;; Go back for more 20$: ADC R4 ;;; Add in last bit BIC #177776,R4 ;;; Get only last bit ASL R4 ;;; Put it in correct place MOV #STCS,(R5) ;;; Select register again MOV R4,2(R5) ;;; Set parity bit TST (SP)+ ;;; Get rid of zero word MOV #STTE,(R5) ;;; Get transmit enable register MOV (SP)+,2(R5) ;;; Load the register MTPS (SP)+ ;;; Reset priority RETURN .SBTTL $IISIE, Set Interprocessor Interrupt Enable ;+ ; **-$IISIE- Set Interprocessor Interrupt enable. ; ; This routine will clear out the status registers of the interprocessor ; interrupt device and then set the interrupt enable. ; ; Inputs: ; ; None. ; ; Outputs: ; ; None. ; ; Registers R0, R1, R2, and R3 are preserved. ;- $IISIE::CALL $IIKRB ; Get IIST KRB addr if onl, else return MFPS -(SP) ; Save priority BISB K.PRI(R4),@#PS ; Raise, don't lower, priority MOV (R4),R4 ;;; Get IIST CSR address MOV #PGCS,(R4) ;;; Select program CSR CLR 2(R4) ;;; Clear it out MOV #177777,R5 ;;; Set word to clear out status bits MOV #EXC,(R4) ;;; Select exception register MOV R5,2(R4) ;;; Clear it out MOV #DCF,(R4) ;;; Select dc/lo register MOV R5,2(R4) ;;; Clear it out MOV #PGF,(R4) ;;; Select program flag register MOV R5,2(R4) ;;; Clear it out MOV #PGCS,(R4) ;;; Select CSR MOV #IE,2(R4) ;;; Set interrupt enable MTPS (SP)+ ;;; Restore priority RETURN .SBTTL $DISAN, Disable all sanity timers ;+ ; **-$DISAN- Disable all sanity timers ; ; This routine clears $stenb and then $STTIC, disabling the sanity ; Timer for the CPU on which it is called. it should be called from ; Each processor before doing a long non-interruptible sequence such ; As crash or parity error stop. ; ; Inputs: ; None ; ; Outputs: ; None ; ; All registers are preserved ;- $DISAN::CALL $SAVNR ; Save registers that get clobbered CLR $STENB ; Set to disable all timers .SBTTL $STTIC, Sanity timer interrupt processing ;+ ; **-$STTIC- Sanity timer interrupt processing. ; ; This routine is designed to be called at every tick on every CPU. ; It will update the sanity timer on the particular processor, and ; will stop the timer if necessary. ; ; Inputs: ; ; This routine is designed to be called from code executing ; at a priority as high as or higher than that of the IIST. ; ; Outputs: ; ; None. ; ; Registers R0, R1, R2, and R3 preserved. ;- $STTIC:: ; Reference label CACHE$ SAVE,BYPASS ; Bypass cache to look at real flags .IF DF X$$ACC&A$$CNT&XA$$MD ;+ ; Handle clock interrupt processing of CPU activities ; ; The layout of the processor mode counters are: ; Word 0,1: Kernel mode ; 2,3: Super/User mode ; 4,5: Idle loop activity ; 6,7: Waiting for executive lock (mutex wait) ;- MOVB $PROCN,R4 ; get the CPU index ASH #4,R4 ; and create the right offset ADD #140002+B.CPAT,R4 ; adjust to our CPU specific block MOV #2*4,R5 ; index for idle counters TSTB $IDLFL ; are we in the idle loop? BGT 3$ ; if GT, yes, handle it ... MOV @#PS,R5 ; get the current PS word BIC #^C<10000>,R5 ; clean down to the previous mode super/user ASH #-10.,R5 ; shift the status down to the low bits BNE 3$ ; if NE, we're in User/super mode ;+ ; See if we're pending for $EXECL, if so flag waiting for lock ;- BIT $CPBIT,$EXECL+4 ; see if we are waiting for exec lock BEQ 3$ ; nope, normal kernel mode activity MOV #3*4,R5 ; indicate waiting for exec lock 3$: ADD R5,R4 ; and select the correct word MOV R0,-(SP) ; save R0 MOV R4,R0 ; shift info for accounting CALL $ACINC ; have accounting do the increments ... .ENDC ; X$$ACC&A$$CNT&XA$$MD 5$: TST $STFLG ; Any reason to process sanity timers ? BEQ 30$ ; If EQ eq 10$: CALL $IIKRB ; Get IIST KRB addr if onl, else return ; ******************************* IIST debugging code ***************** ; ; Find out if the IIST is locked up. to do this we will see if the ; IP!IE bits are set for 10 times in a row. If they are, we will ; toggle the IE bit. ; 15$: MOV (R4),R5 ; Get CSR address MOV #PGCS,(R5) ; Select CSR MOV #IE!IP,-(SP) ; See if both bits set BIC 2(R5),(SP)+ ; Are they both set? BNE 16$ ; If NE ne INC K.CRQ(R4) ; Show one more time that ie!ip set CMP K.CRQ(R4),#10 ; Too many? BLE 18$ ; If le no, do nothing this time ;+ ; IIST is locked up. Clear and reenable the IE bit in PGCS. ;- MOV #PGCS,(R5) ; Select the register CLR 2(R5) ; Clear IE MOV #PGCS,(R5) ; Select the register again BIS #IE,2(R5) ; Set IE again 16$: CLR K.CRQ(R4) ; Start the count over again 18$: ; Reference label ; ******************************* end of IIST debugging code ********** MOV (R4),R4 ; Get CSR address MOV #STCS,(R4) ; Select sanity timer BIT $CPBIT,$STENB ; Should we update and enable sanity timer ; On this CPU? BEQ 20$ ; If EQ eq BIC #4,2(R4) ; Turn off sanity timer lockout always MOV #STCS,(R4) ; Re-select sanity timer register MOV #177401,-(SP) ; Set mask for longest timer interval BIT $CPBIT,$STALR ; Should we enable alarm and lockout BEQ 19$ ; If EQ eq BIS #4,(SP) ; Set alarm enable into mask 19$: BIS (SP)+,2(R4) ; Enable sanity timer for longest interval CACHE$ UNSAVE ; Reset prior state of cache RETURN 20$: BIC #5,2(R4) ; Clear sanity timer counter BIC $CPBIT,$STFLG ; Clear timer processing flag 30$: CACHE$ UNSAVE ; Reset prior state of cache RETURN .SBTTL $IIOPN, Open up the IIST to the rest of the world ;+ ; **-$IIOPN- Enable the IIST to the rest of the world. ; ; This routine will perform a master clear of the IIST when this ; processor goes offline. This will allow another processor to ; boot and interrupt this one at a later time. It will also place ; the IIST KRB offline in the running system. ; ; Inputs: ; ; none. ; ; Outputs: ; ; none. ; ; Registers R0, R1, R2, and R3 are preserved. ;- $IIOPN::CALL $IIKRB ; Get IIST KRB addr if onl, else return MFPS -(SP) ; Save current priority BIS #KS.OFL,K.STS(R4) ; Put IIST KRB offline BISB K.PRI(R4),@#PS ; Raise priority to highest point MOV (R4),-(SP) ; extract the IIST CSR address BIT #KS.EXT,K.STS(R4) ; do we have an auxillary IIST? BEQ 20$ ; if EQ, nope, don't reset it ... BIC #KS.EXT,K.STS(R4) ; clear out the secondary IIST status BIS #100000,@(SP) ; Clear out the primary IIST completely ADD #4,(SP) ; adjust to the secondary IIST 20$: BIS #100000,@(SP)+ ; Clear out IIST completely! MTPS (SP)+ ; Restore priority RETURN .SBTTL $IIKRB, Get address of IIST KRB ;+ ; **-$IIKRB- Get IIST KRB address if online. ; ; This routine will get the KRB address of the IIST for this processor ; and will determine if the KRB shows online status. If it does, the ; routine will return to the caller. If it does not, the routine will ; return to the caller's caller. ; ; Inputs: ; ; 0(SP)= Return address to caller. ; 2(SP)= Return address to caller's caller. ; ; Outputs: ; ; If IIST for this CPU is online: ; R4 = KRB address. ; return to caller. ; Else ; R4 = undefined. ; return to caller's caller. ; ; R4 is destroyed. ;- $IIKRB::MOVB $PROC2,R4 ; Get this processors processor number MOV $IICTB(R4),R4 ; Get KRB address for this IIST BIT #KS.OFL,K.STS(R4) ; Is it online? BEQ 10$ ; If EQ eq TST (SP)+ ; Remove callers return 10$: RETURN .SBTTL $IINOT, Interrupt all online CPUs and wait for ack .SBTTL $IISFA, Send function and wait for ack ;+ ; **-$IINOT- Interrupt all online CPUs and wait for acknowledgement. ; **-$IISFA- Send specific function to all online CPUs and wait for ack. ; ; This routine will interrupt all online CPUs and wait for their ; acknowledgement of the function desired. $IISFA will send a function ; passed as an argument, while $IINOT will send a nop function just ; to make sure that the other processors can hear this one. ; ; Inputs: ; ; R2 = Function code ($IISFA only). ; ; Outputs: ; ; R2 = Processors who didn't acknowledge function (if any). ; ; R4 and R5 are preserved. ;- $IINOT::MOV #MP.NOP,R2 ; Set NOP function $IISFA::MOV $URMST,R1 ; Get online processors BIC $CPMSK,R1 ; Make it CPU's only BIC $CPBIT,R1 ; Not ourselves BNE $IIWAK ; If NE, we have someone to send to CLR R2 ; Show everything is ok RETURN .SBTTL $IIWAK, Send function and wait for ack ;+ ; **-$IIWAK- Send function and wait for acknowledgement. ; ; This routine will use $IIFNX to transmit a function to ; a number of processors, and it will wait a specified interval ; of time for those processors to clear out the function bit ; from their function table. if they do not clear out the ; function within that time, this routine will return ; a error status, and the processor mask(s) for the CPUs that ; haven't done their jobs. ; ; Inputs: ; ; R1 = Mask of processors to function. ; R2 = Function mask. ; ; Outputs: ; ; Processors have received the function. ; ; R2 = CPUs who didn't ack the function (if any). ; ; Registers R1, R4, and R5 are preserved. ;- $IIWAK::MOV R2,-(SP) ; Save the function mask CALL $IIFNX ; Transmit the function to the other CPUs MOV (SP)+,R3 ; Restore the function mask to r3 MOV R4,-(SP) ; Save r4 for caller CLR -(SP) ; Create timeout counters on stack CLR -(SP) ; Timeout is double precision MOV R1,R2 ; Copy interrupted CPU mask ;+ ; Outer loop -- Set up to scan thru the whole table again ;- 10$: MOV #$MPTAB,R0 ; Initialize pointer to top of table MOV #1,R4 ; Set up clear bit mask ;+ ; Inner loop -- Loop through $MPTAB to see if processor has cleared bit ;- 20$: CACHE$ BYPASS ; Look at value of real bit MOV (R0)+,-(SP) ; Get value of switch table for next CPU CACHE$ RESTOR ; Go back to fAST execution BIT R3,(SP)+ ; Has CPU cleared bit yet? BNE 30$ ; If NE, no processor has not acked function BIC R4,R2 ; Clear out CPU bit BEQ 40$ 30$: ASL R4 ; Move bit clear bit left BIC $CPMSK,R4 ; Only deal with CPUs BNE 20$ ; If NE, more CPU's to check ADD #1,2(SP) ; Count of failures to communicate ADC (SP) ; High order word of dbl precision CMP #1,(SP) ; Should we give up now? BGT 10$ ; If GT, nope, check again 40$: CMP (SP)+,(SP)+ ; Clean timeout counter off stack MOV (SP)+,R4 ; Restore R4 for caller 50$: RETURN .DSABL LSB .SBTTL $IISVC, Process function, and interrupt next CPU ;+ ; **-$IISVC- Interprocessor Interrupt pending URM service. ; ; This routine is used to take the pending URM interrupt mask in ; $IIPND and convert them to pending CPU interrupts in $IICPU. ; It will then interrupt the next processor round robin, using ; $IINXT. ; ; Inputs: ; ; $IIPND contains mask bits for all URMs needing service. ; ; Outputs. ; ; The URM bits in $IIPND have been converted into CPU bits in ; $IICPU, and using $IINXT a particular CPU has been selected ; to be interrupted. $IIXMT has been called to interrupt the ; selected CPU. ; ; No registers are preserved. ;- .ENABL LSB $IISVC::CACHE$ BYPASS ; Figure out work to do MOV $IIPND,R1 ; Get pending URM mask BIC $IICPU,R1 ; Clear out those already interrupted CACHE$ RESTOR TST R1 ; Any work not already interrupted? BEQ 80$ ; If EQ eq MOV #$URMTB,R0 ; Start scan thru CPU URM connection tbl CLR R3 ; Clear out accumulator for CPU bits 10$: BIT R1,(R0)+ ; Are any pending runs on this CPU? BEQ 20$ ; If EQ, no, don't interrupt this processor BIS $BTMSK-$URMTB-2(R0),R3 ; Yes -- set this CPU's bit 20$: CMP #$URMTB+,R0 ; Is it end of table? BHI 10$ ; If GT gt TST R3 ; Any CPU's to interrupt BNE 25$ ; If NE, yes, process the functions pending ;+ ; No CPUs to interrupt. We shouldn't be here ;- BIC $CPMSK,R1 ; is this a CPU URM? BEQ 80$ ; if EQ, powerfail on external buss BGCK$A BF.MP,BE.UNP,FATAL ; Some URM not connected to CPU ;+ ; Interrupt next CPU in order. ; ; Special note: $IINXT contains a pointer into $BTMSK. It is a ; common pointer, yet is both read without bypass (possbily ; encountering stale data), and set without locking anything ; (possibly causing multiple updates). In both cases, only a slight ; perturbation to the round robin fairness doctrine results. ; ; It is also possible that two processors may interrupt the same ; processor, but this is unlikely so no explicit check is made. ;- 25$: MOV $IINXT,R2 ; Get pointer into $BTMSK for round robin 30$: BIT (R2)+,R3 ; Does this CPU need an interrupt BNE 40$ ; If NE, yes, interrupt this processor CMP #$BTMSK+,R2 ; End of table? BHI 30$ ; If HI, nope, pointer is valid MOV #$BTMSK,R2 ; Start at top of table again BR 30$ ; Go back 40$: MOV -(R2),R1 ; Get the CPU's bit for $IIXMT MOV R2,$IINXT ; Save pointer into $BTMSK for rnd robin MFPS -(SP) ; Save priority MTPS #PR7 ; Raise priority to lock LOCK$ $FORKL,SPIN BIS $URMTB-$BTMSK(R2),$IICPU ;;; Show these URMs interrupted ULOCK$ $FORKL,SPIN MTPS (SP)+ ; Restore priority .SBTTL $IINXT, IIST Interrupt transmit ;+ ; **-$IIXMT- Interprocessor Interrupt transmit. ; ; This routine will interrupt the CPU specified by bit mask in ; R1, using the interprocessor interrupt. ; ; Inputs: ; ; R1=processor bit mask for processor(s) to interrupt. ; ; Outputs: ; ; None. ; ; R1, R4, and R5 are preserved across call. ;- $IIXMT::MOVB $PROC2,R0 ; Get processor number * 2 MOV $IICTB(R0),R3 ; Get KRB address of II BIT #KS.OFL,K.STS(R3) ; Is IIST for this CPU offline? BNE 80$ ; If NE, yes, don't interrupt this processor ;+ ; Calculate parity for the processor mask. ;- MOV R1,R2 ; Duplicate processor mask MOV #1,R0 ; Initialize odd parity in r0 CLC ; Clean out carry ROR R2 ; Put first bit in carry -- dont sign ex BEQ 60$ ; No bits left! ADC R0 ; Bump parity count 50$: ASR R2 ; Put next bit in carry BEQ 60$ ; If EQ, end of accumulation ADC R0 ; Accumulate parity BR 50$ ; Go back for more bits 60$: ADC R0 ; Add in last bit BIC #177776,R0 ; We want parity bit ASL R0 ; Justify in parity position BIS #,R0 ; Add other important bits MOV (R3),R2 ; Get CSR of the IIST MFPS -(SP) ; Save priority BISB K.PRI(R3),@#PS ; Raise, don't lower priority CLR R3 ; Initialize infinite loop counter MOV #PGTE,(R2) ;;; Select device register MOV R1,2(R2) ;;; Set it up 70$: MOV #PGCS,(R2) ;;; Select ii CSR ADD #1,R3 ; Count number of times we have looped BCS 75$ ; If overflow, forget the IIST BIT #RDY,2(R2) ;;; Is it ready BEQ 70$ ;;; If EQ eq MOV #PGCS,(R2) ;;; Yes -- find register and go MOV R0,2(R2) ;;; Yes -- load function and go TALLY$ B.IPSN,XA$$IP,CPU ; Count an IP Intr sent 75$: MTPS (SP)+ ; Restore priority 80$: RETURN .SBTTL $IBXMT, Interprocessor boot transmit ;+ ; **-$IBXMT- Interprocessor boot transmit. ; ; This routine will boot the processors specified by the bit mask ; in R1. ; ; Inputs: ; ; R1 = Processor bit mask of processors to boot. ; ; Outputs: ; ; None. ; ; R1, R4, and R5 are preserved across call. ;- $IBXMT::SWAB R1 ; Place bits in correct place CALL $IIXMT ; Transmit boot requests SWAB R1 ; Restore R1 to original purity RETURN ;+ ; Misc. interrupt service special processing ;- ;+ ; Jump off to processor entry. ;- $CPBGN::NOP ; Let operator continue (debugging) JMP $PENT ; Go to processor entry ;+ ; Error sensed in IIST flag registers. ;- ERROR: BGCK$A BF.MP,BE.FHW,FATAL ; Can't handle this yet ;+ ; No errors or interrupts -- why are we here ;- NOINT: BGCK$A BF.MP,BE.NIN,FATAL ; No implementation yet .DSABL LSB .SBTTL $IIINT, Interprocessor Interrupt interrupt service ;+ ; **-$IIINT- Interrprocessor Interrupt interrput service. ; ; This routine accepts incomming interrupts from the IIST. It ; will, if the proper bit is clear in $IIWAT, report reception ; Of the interrupt to all waiting processors and load its ; Interrupt masks. otherwise, it will simply exit through ; $FORK through $DIRXT. Note: the interrupt vector for the II must ; uniquely determine the CSR address (i.e. csr=f(vec)) for the ; initialization code to work properly! ; ; Inputs: ; ; PS=controller id in lower 4 bits. ; ; Outputs: ; ; None. ; ; Executes at interrupt level, and at exec level. Observes proper ; register conventions for those levels. ;- .ENABL LSB $IIINT::MFPS -(SP) ;;; Save condition code bits ;+ ; This is a possible entry for CPU startup, when the processor ; starting up is interrupted out of the bootstrap and thru cpa's ; local memory (and vectors). If CPA is online at the time, then ; its IIST vector points to this routine. Since the bootstrap ; turns off mapping prior to enabling interrupts, the fact that ; the mapping is turned off is a signal to this routine that this ; is a CPU startup, and we should jump to $CPBGN (and thence to ; $PENT). ;- BIT #1,SR0 ;;; Is mapping enabled? BEQ $CPBGN ;;; If EQ, no, must be processor startup MTPS (SP)+ ;;; Restore PS condition code bits INTSV$ II,PR6,M$$PRO ;;; Do normal interrupt save MOV (R5),R4 ;;; Get CSR address of IIST ;+ ; If a secondary IIST is present, we will check for an intr pending, ; and if so, call the primary service, and return back to do it again ... ; ; Note: if the interrupt is pending, the stack will be: ; ; 4(SP) - Return to $INTXT ; 2(SP) - KRB address ; 0(SP) - Return to process secondary IIST ;- BIT #KS.EXT,K.STS(R5) ;;; do we have a secondary IIST? BEQ 3$ ;;; If EQ, nope, don't check ... MOV #PGCS,4(R4) ;;; check the secondary IIST CSR MOV 6(R4),-(SP) ;;; get the secondary PGCS BIC #^C,(SP) ;;; clear all but desired bits CMP (SP)+,# ;;; are both bits set? BNE 3$ ;;; if NE, nothing pending on the secondary MOV R5,-(SP) ;;; save the KRB address CALL 3$ ;;; process the primary controller intr. MOV (SP),R5 ;;; restore the KRB address MOV (R5),R4 ;;; get the primary CSR address ADD #4,R4 ;;; select the secondary IIST INC (SP) ;;; and flag as secondary IIST BR 4$ ;;; and process the interrupt 3$: TALLY$ B.IPRC,XA$$IP,CPU ; Count an IP Intr Rcvd ; ********************************* IIST debugging code *************** CLR K.CRQ(R5) ;;; Clear out counter for $STTIC ; ********************************* end IIST debugging code *********** MOV R5,-(SP) ;;; Save KRB on stack for later 4$: MOV #EXC,(R4) ;;; Select exception register MOV 2(R4),R5 ;;; Get all bits MOV #EXC,(R4) ;;; Select exception register MOV R5,2(R4) ;;; Clear all received BIC #177400,R5 ;;; Clear out all but the rte errors BEQ 5$ ;;; If EQ, no errors observed MOV (SP),R5 ;;; Get KRB address for IIST krb INC K.CRQ+2(R5) ;;; Increment rte error counter 5$: MOV #DCF,(R4) ;;; Select DC / lo flags register MOV 2(R4),R5 ;;; Get all bits MOV #DCF,(R4) ;;; Select DC / lo flags register MOV R5,2(R4) ;;; Clear all bits BIT #1,(SP) ;;; is this the secondary IIST? BNE 10$ ;;; if NE, yes, don't adjust any masks BIC #177400,R5 ;;; Use only the DCF bits (not brk) BEQ 10$ ;;; If no DCF changes MOV R4,-(SP) ;;; Save CSR on stack CALL $IISLM ;;; Set the local interrupt masks MOV (SP)+,R4 ;;; Restore R4 10$: MOV #STF,(R4) ;;; Select sanity timer flag register MOV 2(R4),R5 ;;; Get flags MOV #STF,(R4) ;;; Select register again MOV R5,2(R4) ;;; Clear them out BEQ 20$ ;;; If EQ, interrupt not due to sanity timer BIC #177760,R5 ;;; Make it CPU's only ROR (SP)+ ;;; primary or secondary IIST? BCC 15$ ;;; if CC, primary IIST BGCK$A BF.SAN,BE.IDC,DIRECT2 ;;; Sanity timer error 15$: BGCK$A BF.SAN,BE.FHW,DIRECT2 ;;; Crash with sanity timer message 20$: MOV #PGF,(R4) ;;; Select interrupt received mask reg MOV 2(R4),R5 ;;; Get mask of those who interrupted MOV #PGF,(R4) ;;; Select PGF again MOV R5,2(R4) ;;; Clear those bits to show reception BEQ 30$ ;;; if EQ, nothing in the flags byte BIT #1,(SP) ;;; is this the secondary IIST BEQ 30$ ;;; if EQ, nope, process the PGF flags DEC (SP) ;;; reset R4 to be the KRB address MOV R5,-(SP) ;; save our mask field MOV 2(SP),R5 ;;; restore our KRB address MOV (R5),R4 ;;; extract the CSR address ADD #4,R4 ;;; point to the secondary IIST CSR BIT #KS.POE,K.STS(R5) ;;; parallel operation enabled? BNE 32$ ;;; if NE, yes, treat function as real BIT #KS.UOP,K.STS(R5) ;;; is some task handling PGF? BEQ 37$ ;;; if EQ, nope, just reset IE ;+ ; Dispatch the PGF flags to the requesting task ... ;- SWAB (SP) ;;; save interrupting CPUs in the high byte CLRB (SP) ;;; and clear the low byte CALL 38$ ;;; re-enable interrupts ... BR 35$ ;;; and rejoin common code 30$: MOV R5,-(SP) ;;; Save those who interrupted 32$: CALL 38$ ;;; reset the interrupt enable, after cleanup CACHE$ BYPASS MOV @$MPSWT,R5 ; Get function table CACHE$ RESTOR BIC #MP.INT,R5 ; Only processor those to be done at int lvl BEQ 35$ ; If EQ, not an interrupt function MOV (SP),R4 ; Get those who interrupted CALL $IIFNC ; Execute functions 35$: MOV (SP)+,R5 ; Get interrupt mask MOV (SP)+,R4 ;;; Get KRB address back TST K.FRK+2(R4) ;;; Have we a fork queued? BEQ 40$ ;;; If EQ, nope, go fork ... BIS R5,K.FRK+4(R4) ;;; Add our CPUs to current fork RETURN 37$: CMP (SP)+,(SP)+ ;;; clean up the stack ;+ ; Nothing is pending for our CPU, just clean ; up and return, after resetting interrupt enable ;- 38$: MOV #PGCS,(R4) ;;; Select IIST CSR register CLR 2(R4) ;;; Clear it out MOV #PGCS,(R4) ;;; Select IIST CSR register MOV #IE,2(R4) ;;; Set interrupt enable RETURN ;;; to caller ;+ ; Queue fork block ;- 40$: ADD #K.FRK+6,R4 ;;; Point to last word + 2 CALL $FORK1 ;;; Exit thru fork routine ;+ ; Executive level service. ;- CACHE$ BYPASS ; Force cache bypass SUB #,R3 ; Create KRB address MTPS K.PRI(R3) ; Raise priority to block II interrupt service CLR K.FRK+2(R3) ;;; Show fork block not in use BIS K.FRK+4(R3),R5 ;;; Get any additional bits from window MTPS #0 ;;; Lower priority CLR R4 ; Create an accumulator BISB R5,R4 ; Put interrupt mask in proper place SWAB R5 ; Get the high byte, and process if needed BIC #177400,R5 ; Isolate only secondary activity BEQ 45$ ; if EQ, nothing to notify task about ... MOV $VERTK,R0 ; do we have a task to queue to? BEQ 45$ ; if EQ, nope, skip this ... TST T.STAT(R0) ; is the task running? BMI 45$ ; if MI, nope, don't do anything ... ;+ ; Call the processing task, and allow it to process the remote system ; interrupt, if desired ... ;- MOV $NXTLK,KISAR5 ; Map to the task bias desired .IF DF,K$$DAS MOV $NXTLK,KINAR5 ; and also in I-space .ENDC ;DF,K$$DAS MOV R4,-(SP) ; save our primary IIST mask word ... CALL @$NXTLK+2 ; and call the desired subroutine MOV (SP)+,R4 ; restore the primary IIST mask 45$: MOV @$MPSWT,R5 ; Get function mask CACHE$ RESTOR TST R5 ; Process functions BEQ 50$ ; If EQ, no functions to process CALL $IIFNC 50$: RETURN .DSABL LSB .SBTTL $IIFNC, Execute interprocessor function ;+ ; **-$IIFNC- Execute Interprocessor Function. ; ; This routine will take a function mask in R5 and execute all ; functions corresponding to the bits set in the mask. It will ; use the jump table at $MPDSP. ; ; Inputs: ; ; R4=processors that have interrupted this one. ; R5=function mask for this processor. ; ; Outputs: ; ; All of the functions specified in the function mask have ; been executed. ; ; R0, R1, R2, R3 are preserved. ;- $IIFNC::MOV R3,-(SP) ; Save R3 MOV R4,-(SP) ; Save R4 for our use later MOV #100000,R4 ; Set up clear mask MOV #$MPDSP,R3 ; Set start of jump table 10$: ASL R5 ; Pick up next bit from left side BCC 20$ ; If CC, don't dispatch this function ;+ ; We found a function for this bit ;- MOV R5,-(SP) ; Save R5 MOV R4,-(SP) ; Save R4 MOV R3,-(SP) ; Save R3 ;+ ; Call function subroutine from dispatch table. ; ; The function subroutines called from interrupt level have ; R3, R4, and R5 available for use. Those called from exec ; level have all registers available. ; ; Inputs: ; ; R4=mask of processors that interrupted. ;- MOV 6(SP),R4 ; Put processor interrupt mask in R4 CALL @(R3) ; Call subroutine from dispatch table MOV (SP)+,R3 ; Restore R3 MOV (SP)+,R4 ; Restore R4 MFPS -(SP) ; Save priority MTPS #PR7 ; Don't get interrupted during lock LOCK$ $IIFNL,SPIN ;;; Lock the function table BIC R4,@$MPSWT ;;; Clear out our function ULOCK$ $IIFNL,SPIN ;;; Unlock the function table MTPS (SP)+ ;;; Restore the priority MOV (SP)+,R5 ; Restore R5 20$: BEQ 30$ ; If EQ, no more functions to process TST (R3)+ ; Bump jump table pointer ROR R4 ; Point at next bit to clear BNE 10$ ; If NE, bit hasn't shifted into CC-C ; (This will never fall thru - R5 = 0 first) 30$: MOV (SP)+,R4 ; Restore R4 (not really necessary -- MOV (SP)+,R3 ; Restore R3 RETURN ;+ ; **-$IIFNX- Interprocessor function transmit. ; ; This routine will load the bit in the function mask for the ; appropriate processor and will interrupt the processor(s) ; directly if the function can be processed at interrupt level, ; otherwise the processor will be interrupted to go to exec level ; and process the function. ; ; Inputs: ; ; R1=mask of processors to function. ; R2=function mask. ; ; Outputs: ; ; Processors have recieved the function. ; ; Registers R1, R4, and R5 are preserved. ;- $IIFNX::MOV R1,R0 ; Duplicate process word MOV #$MPTAB,R3 ; Point to table 10$: CLC ; Make following ror work write ROR R0 ; Put next CPU bit in carry BCC 20$ ; If CC, don't need to interrupt this CPU ;+ ; We have found a CPU bit on. Place the function mask into his function ; word. ;- MFPS -(SP) ; Save priority MTPS #PR7 ; Dont get interrupted during lock LOCK$ $IIFNL,SPIN ;;; Lock the function table BIS R2,(R3) ;;; Set the function ULOCK$ $IIFNL,SPIN ;;; Unlock the function table MTPS (SP)+ ;;; Restore priority TST R0 ; Set the condition code bits 20$: BEQ 30$ ; If EQ, nothing left TST (R3)+ ; Point to next word in function table BR 10$ ; Go back for more 30$: BIC #MP.INT,R2 ; Special interrupt level function? BEQ 40$ ; If EQ, nope, fork to process the function ;+ ; This function is one of those which is processed in the interrupt ; service routine of the interprocessor interrupt. Since the CPUs ; involved (if more than one) don't have to be locked into the exec ; to process the function, then we will interrupt them all immediately ; and allow them to process the function in parallel. ;- CALL $IIXMT ; Interrupt processors RETURN ;+ ; In the following case, the processors must be in the executive to ; process the function. We consider this another reason to interrupt ; the processor in the normal, round robin scheme of things. ;- 40$: MFPS -(SP) ; Save priority MTPS #PR7 ; No interrupts during locked period LOCK$ $FORKL,SPIN ;;; Lock the fork list BIS R1,$IIPND ;;; Set the CPU's we want to interrupt ULOCK$ $FORKL,SPIN ;;; Unlock the fork list MTPS (SP)+ ;;; Restore priority RETURN .ENDC .END